YES 5.122
H-Termination proof of /home/matraf/haskell/eval_FullyBlown_Fast/List.hs
H-Termination of the given Haskell-Program with start terms could successfully be proven:
↳ HASKELL
↳ LR
mainModule List
| ((group :: [Char] -> [[Char]]) :: [Char] -> [[Char]]) |
module List where
| import qualified Maybe import qualified Prelude
|
| group :: Eq a => [a] -> [[a]]
|
| groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy | _ [] | = | [] |
groupBy | eq (x : xs) | = |
(x : ys) : groupBy eq zs | where |
|
|
|
module Maybe where
| import qualified List import qualified Prelude
|
Lambda Reductions:
The following Lambda expression
\(_,zs)→zs
is transformed to
The following Lambda expression
\(ys,_)→ys
is transformed to
The following Lambda expression
\(_,zs)→zs
is transformed to
The following Lambda expression
\(ys,_)→ys
is transformed to
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
mainModule List
| ((group :: [Char] -> [[Char]]) :: [Char] -> [[Char]]) |
module List where
| import qualified Maybe import qualified Prelude
|
| group :: Eq a => [a] -> [[a]]
|
| groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy | _ [] | = | [] |
groupBy | eq (x : xs) | = |
(x : ys) : groupBy eq zs | where |
|
|
|
module Maybe where
| import qualified List import qualified Prelude
|
Replaced joker patterns by fresh variables and removed binding patterns.
Binding Reductions:
The bind variable of the following binding Pattern
xs@(wu : wv)
is replaced by the following term
wu : wv
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
mainModule List
| ((group :: [Char] -> [[Char]]) :: [Char] -> [[Char]]) |
module List where
| import qualified Maybe import qualified Prelude
|
| group :: Eq a => [a] -> [[a]]
|
| groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy | vw [] | = | [] |
groupBy | eq (x : xs) | = |
(x : ys) : groupBy eq zs | where |
|
|
|
module Maybe where
| import qualified List import qualified Prelude
|
Cond Reductions:
The following Function with conditions
is transformed to
undefined0 | True | = undefined |
undefined1 | | = undefined0 False |
The following Function with conditions
span | p [] | = ([],[]) |
span | p (wu : wv) | |
is transformed to
span | p [] | = span3 p [] |
span | p (wu : wv) | = span2 p (wu : wv) |
span2 | p (wu : wv) | =
span1 p wu wv (p wu) |
where |
span0 | p wu wv True | = ([],wu : wv) |
|
|
span1 | p wu wv True | = (wu : ys,zs) |
span1 | p wu wv False | = span0 p wu wv otherwise |
|
| |
| |
| |
| |
| |
|
span3 | p [] | = ([],[]) |
span3 | xv xw | = span2 xv xw |
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
mainModule List
| ((group :: [Char] -> [[Char]]) :: [Char] -> [[Char]]) |
module List where
| import qualified Maybe import qualified Prelude
|
| group :: Eq a => [a] -> [[a]]
|
| groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy | vw [] | = | [] |
groupBy | eq (x : xs) | = |
(x : ys) : groupBy eq zs | where |
|
|
|
module Maybe where
| import qualified List import qualified Prelude
|
Let/Where Reductions:
The bindings of the following Let/Where expression
(x : ys) : groupBy eq zs |
where | |
| |
| |
| |
| |
are unpacked to the following functions on top level
groupByVv10 | xx xy xz | = span (xx xy) xz |
groupByZs | xx xy xz | = groupByZs0 xx xy xz (groupByVv10 xx xy xz) |
groupByYs0 | xx xy xz (ys,vx) | = ys |
groupByZs0 | xx xy xz (vy,zs) | = zs |
groupByYs | xx xy xz | = groupByYs0 xx xy xz (groupByVv10 xx xy xz) |
The bindings of the following Let/Where expression
span1 p wu wv (p wu) |
where |
span0 | p wu wv True | = ([],wu : wv) |
|
|
span1 | p wu wv True | = (wu : ys,zs) |
span1 | p wu wv False | = span0 p wu wv otherwise |
|
| |
| |
| |
| |
| |
are unpacked to the following functions on top level
span2Span1 | yu yv p wu wv True | = (wu : span2Ys yu yv,span2Zs yu yv) |
span2Span1 | yu yv p wu wv False | = span2Span0 yu yv p wu wv otherwise |
span2Zs1 | yu yv (ww,zs) | = zs |
span2Zs | yu yv | = span2Zs1 yu yv (span2Vu43 yu yv) |
span2Vu43 | yu yv | = span yu yv |
span2Span0 | yu yv p wu wv True | = ([],wu : wv) |
span2Ys1 | yu yv (ys,wx) | = ys |
span2Ys | yu yv | = span2Ys1 yu yv (span2Vu43 yu yv) |
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
mainModule List
| (group :: [Char] -> [[Char]]) |
module List where
| import qualified Maybe import qualified Prelude
|
| group :: Eq a => [a] -> [[a]]
|
| groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy | vw [] | = | [] |
groupBy | eq (x : xs) | = | (x : groupByYs eq x xs) : groupBy eq (groupByZs eq x xs) |
|
|
groupByVv10 | xx xy xz | = | span (xx xy) xz |
|
|
groupByYs | xx xy xz | = | groupByYs0 xx xy xz (groupByVv10 xx xy xz) |
|
|
groupByYs0 | xx xy xz (ys,vx) | = | ys |
|
|
groupByZs | xx xy xz | = | groupByZs0 xx xy xz (groupByVv10 xx xy xz) |
|
|
groupByZs0 | xx xy xz (vy,zs) | = | zs |
|
module Maybe where
| import qualified List import qualified Prelude
|
Haskell To QDPs
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
↳ AND
↳ QDP
↳ QDPSizeChangeProof
↳ QDP
↳ QDP
↳ QDP
↳ QDP
Q DP problem:
The TRS P consists of the following rules:
new_span2Ys(:(Char(Zero), yw3111)) → new_span2Zs(yw3111)
new_span2Ys(:(Char(Zero), yw3111)) → new_span2Ys(yw3111)
new_span2Zs(:(Char(Zero), yw3111)) → new_span2Ys(yw3111)
new_span2Zs(:(Char(Zero), yw3111)) → new_span2Zs(yw3111)
R is empty.
Q is empty.
We have to consider all minimal (P,Q,R)-chains.
By using the subterm criterion [20] together with the size-change analysis [32] we have proven that there are no infinite chains for this DP problem. From the DPs we obtained the following set of size-change graphs:
- new_span2Zs(:(Char(Zero), yw3111)) → new_span2Ys(yw3111)
The graph contains the following edges 1 > 1
- new_span2Zs(:(Char(Zero), yw3111)) → new_span2Zs(yw3111)
The graph contains the following edges 1 > 1
- new_span2Ys(:(Char(Zero), yw3111)) → new_span2Ys(yw3111)
The graph contains the following edges 1 > 1
- new_span2Ys(:(Char(Zero), yw3111)) → new_span2Zs(yw3111)
The graph contains the following edges 1 > 1
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
↳ AND
↳ QDP
↳ QDP
↳ QDPSizeChangeProof
↳ QDP
↳ QDP
↳ QDP
Q DP problem:
The TRS P consists of the following rules:
new_span2Zs1(yw179, yw180, yw181, Zero, Zero) → new_span2Zs0(yw179, yw181)
new_span2Ys1(yw173, yw174, yw175, Zero, Zero) → new_span2Zs0(yw173, yw175)
new_span2Zs0(yw53, :(Char(Succ(yw55000)), yw551)) → new_span2Zs1(yw53, yw55000, yw551, yw53, yw55000)
new_span2Zs1(yw179, yw180, yw181, Zero, Zero) → new_span2Ys0(yw179, yw181)
new_span2Zs1(yw179, yw180, yw181, Succ(yw1820), Succ(yw1830)) → new_span2Zs1(yw179, yw180, yw181, yw1820, yw1830)
new_span2Ys1(yw173, yw174, yw175, Zero, Zero) → new_span2Ys0(yw173, yw175)
new_span2Ys0(yw39, :(Char(Succ(yw41000)), yw411)) → new_span2Ys1(yw39, yw41000, yw411, yw39, yw41000)
new_span2Ys1(yw173, yw174, yw175, Succ(yw1760), Succ(yw1770)) → new_span2Ys1(yw173, yw174, yw175, yw1760, yw1770)
R is empty.
Q is empty.
We have to consider all minimal (P,Q,R)-chains.
By using the subterm criterion [20] together with the size-change analysis [32] we have proven that there are no infinite chains for this DP problem. From the DPs we obtained the following set of size-change graphs:
- new_span2Zs0(yw53, :(Char(Succ(yw55000)), yw551)) → new_span2Zs1(yw53, yw55000, yw551, yw53, yw55000)
The graph contains the following edges 1 >= 1, 2 > 2, 2 > 3, 1 >= 4, 2 > 5
- new_span2Zs1(yw179, yw180, yw181, Succ(yw1820), Succ(yw1830)) → new_span2Zs1(yw179, yw180, yw181, yw1820, yw1830)
The graph contains the following edges 1 >= 1, 2 >= 2, 3 >= 3, 4 > 4, 5 > 5
- new_span2Ys0(yw39, :(Char(Succ(yw41000)), yw411)) → new_span2Ys1(yw39, yw41000, yw411, yw39, yw41000)
The graph contains the following edges 1 >= 1, 2 > 2, 2 > 3, 1 >= 4, 2 > 5
- new_span2Zs1(yw179, yw180, yw181, Zero, Zero) → new_span2Zs0(yw179, yw181)
The graph contains the following edges 1 >= 1, 3 >= 2
- new_span2Zs1(yw179, yw180, yw181, Zero, Zero) → new_span2Ys0(yw179, yw181)
The graph contains the following edges 1 >= 1, 3 >= 2
- new_span2Ys1(yw173, yw174, yw175, Zero, Zero) → new_span2Zs0(yw173, yw175)
The graph contains the following edges 1 >= 1, 3 >= 2
- new_span2Ys1(yw173, yw174, yw175, Succ(yw1760), Succ(yw1770)) → new_span2Ys1(yw173, yw174, yw175, yw1760, yw1770)
The graph contains the following edges 1 >= 1, 2 >= 2, 3 >= 3, 4 > 4, 5 > 5
- new_span2Ys1(yw173, yw174, yw175, Zero, Zero) → new_span2Ys0(yw173, yw175)
The graph contains the following edges 1 >= 1, 3 >= 2
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
↳ AND
↳ QDP
↳ QDP
↳ QDP
↳ QDPSizeChangeProof
↳ QDP
↳ QDP
Q DP problem:
The TRS P consists of the following rules:
new_groupByZs0(yw90, yw91, yw92, Succ(yw930), Succ(yw940)) → new_groupByZs0(yw90, yw91, yw92, yw930, yw940)
R is empty.
Q is empty.
We have to consider all minimal (P,Q,R)-chains.
By using the subterm criterion [20] together with the size-change analysis [32] we have proven that there are no infinite chains for this DP problem. From the DPs we obtained the following set of size-change graphs:
- new_groupByZs0(yw90, yw91, yw92, Succ(yw930), Succ(yw940)) → new_groupByZs0(yw90, yw91, yw92, yw930, yw940)
The graph contains the following edges 1 >= 1, 2 >= 2, 3 >= 3, 4 > 4, 5 > 5
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
↳ AND
↳ QDP
↳ QDP
↳ QDP
↳ QDP
↳ QDPSizeChangeProof
↳ QDP
Q DP problem:
The TRS P consists of the following rules:
new_groupByYs0(yw68, yw69, yw70, Succ(yw710), Succ(yw720)) → new_groupByYs0(yw68, yw69, yw70, yw710, yw720)
R is empty.
Q is empty.
We have to consider all minimal (P,Q,R)-chains.
By using the subterm criterion [20] together with the size-change analysis [32] we have proven that there are no infinite chains for this DP problem. From the DPs we obtained the following set of size-change graphs:
- new_groupByYs0(yw68, yw69, yw70, Succ(yw710), Succ(yw720)) → new_groupByYs0(yw68, yw69, yw70, yw710, yw720)
The graph contains the following edges 1 >= 1, 2 >= 2, 3 >= 3, 4 > 4, 5 > 5
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
↳ AND
↳ QDP
↳ QDP
↳ QDP
↳ QDP
↳ QDP
↳ QDPOrderProof
Q DP problem:
The TRS P consists of the following rules:
new_groupBy(:(yw30, yw31)) → new_groupBy(new_groupByZs00(yw30, yw31))
The TRS R consists of the following rules:
new_groupByZs00(Char(Zero), :(Char(Succ(yw31000)), yw311)) → :(Char(Succ(yw31000)), yw311)
new_groupByZs00(yw30, []) → []
new_span2Zs11(yw179, yw180, yw181) → :(Char(Succ(yw180)), yw181)
new_span2Zs13(yw179, yw180, yw181, yw187, yw186) → yw186
new_groupByZs03(yw90, yw91, yw92, yw100, yw99) → yw99
new_span2Ys3([]) → []
new_span2Zs3(:(Char(Succ(yw311000)), yw3111)) → :(Char(Succ(yw311000)), yw3111)
new_span2Zs3(:(Char(Zero), yw3111)) → new_span2Zs10(yw3111, new_span2Ys3(yw3111), new_span2Zs3(yw3111))
new_span2Ys2(yw39, :(Char(Succ(yw41000)), yw411)) → new_span2Ys12(yw39, yw41000, yw411, yw39, yw41000)
new_groupByZs02(yw90, yw91, yw92) → :(Char(Succ(yw91)), yw92)
new_span2Ys10(yw173, yw174, yw175) → []
new_groupByZs00(Char(Zero), :(Char(Zero), yw311)) → new_span2Zs3(yw311)
new_groupByZs00(Char(Succ(yw3000)), :(Char(Zero), yw311)) → :(Char(Zero), yw311)
new_groupByZs01(yw90, yw91, yw92, Zero, Zero) → new_groupByZs03(yw90, yw91, yw92, new_span2Ys2(yw90, yw92), new_span2Zs2(yw90, yw92))
new_span2Ys3(:(Char(Zero), yw3111)) → new_span2Ys11(yw3111, new_span2Ys3(yw3111), new_span2Zs3(yw3111))
new_span2Ys13(yw173, yw174, yw175, yw185, yw184) → :(Char(Succ(yw174)), yw185)
new_span2Ys11(yw3111, yw5, yw4) → :(Char(Zero), yw5)
new_span2Ys12(yw173, yw174, yw175, Zero, Succ(yw1770)) → new_span2Ys10(yw173, yw174, yw175)
new_span2Ys12(yw173, yw174, yw175, Succ(yw1760), Zero) → new_span2Ys10(yw173, yw174, yw175)
new_span2Zs2(yw53, :(Char(Succ(yw55000)), yw551)) → new_span2Zs12(yw53, yw55000, yw551, yw53, yw55000)
new_span2Zs12(yw179, yw180, yw181, Zero, Zero) → new_span2Zs13(yw179, yw180, yw181, new_span2Ys2(yw179, yw181), new_span2Zs2(yw179, yw181))
new_groupByZs01(yw90, yw91, yw92, Succ(yw930), Succ(yw940)) → new_groupByZs01(yw90, yw91, yw92, yw930, yw940)
new_span2Zs12(yw179, yw180, yw181, Succ(yw1820), Zero) → new_span2Zs11(yw179, yw180, yw181)
new_span2Zs12(yw179, yw180, yw181, Zero, Succ(yw1830)) → new_span2Zs11(yw179, yw180, yw181)
new_span2Ys2(yw39, :(Char(Zero), yw411)) → []
new_span2Ys3(:(Char(Succ(yw311000)), yw3111)) → []
new_span2Ys2(yw39, []) → []
new_span2Zs3([]) → []
new_groupByZs01(yw90, yw91, yw92, Succ(yw930), Zero) → new_groupByZs02(yw90, yw91, yw92)
new_groupByZs01(yw90, yw91, yw92, Zero, Succ(yw940)) → new_groupByZs02(yw90, yw91, yw92)
new_span2Zs12(yw179, yw180, yw181, Succ(yw1820), Succ(yw1830)) → new_span2Zs12(yw179, yw180, yw181, yw1820, yw1830)
new_span2Ys12(yw173, yw174, yw175, Succ(yw1760), Succ(yw1770)) → new_span2Ys12(yw173, yw174, yw175, yw1760, yw1770)
new_span2Ys12(yw173, yw174, yw175, Zero, Zero) → new_span2Ys13(yw173, yw174, yw175, new_span2Ys2(yw173, yw175), new_span2Zs2(yw173, yw175))
new_span2Zs2(yw53, []) → []
new_span2Zs10(yw3111, yw7, yw6) → yw6
new_groupByZs00(Char(Succ(yw3000)), :(Char(Succ(yw31000)), yw311)) → new_groupByZs01(yw3000, yw31000, yw311, yw3000, yw31000)
new_span2Zs2(yw53, :(Char(Zero), yw551)) → :(Char(Zero), yw551)
The set Q consists of the following terms:
new_span2Ys3(:(Char(Zero), x0))
new_groupByZs01(x0, x1, x2, Zero, Zero)
new_span2Zs12(x0, x1, x2, Succ(x3), Zero)
new_span2Ys2(x0, :(Char(Zero), x1))
new_groupByZs00(x0, [])
new_span2Zs12(x0, x1, x2, Zero, Succ(x3))
new_span2Zs3(:(Char(Zero), x0))
new_span2Zs11(x0, x1, x2)
new_span2Ys3([])
new_span2Zs2(x0, [])
new_groupByZs00(Char(Zero), :(Char(Succ(x0)), x1))
new_span2Zs13(x0, x1, x2, x3, x4)
new_span2Zs2(x0, :(Char(Zero), x1))
new_span2Zs3(:(Char(Succ(x0)), x1))
new_span2Ys12(x0, x1, x2, Zero, Zero)
new_span2Zs12(x0, x1, x2, Zero, Zero)
new_groupByZs00(Char(Zero), :(Char(Zero), x0))
new_span2Zs10(x0, x1, x2)
new_span2Ys12(x0, x1, x2, Zero, Succ(x3))
new_span2Zs2(x0, :(Char(Succ(x1)), x2))
new_groupByZs01(x0, x1, x2, Zero, Succ(x3))
new_span2Zs3([])
new_span2Ys2(x0, :(Char(Succ(x1)), x2))
new_groupByZs03(x0, x1, x2, x3, x4)
new_span2Ys10(x0, x1, x2)
new_span2Ys12(x0, x1, x2, Succ(x3), Zero)
new_groupByZs00(Char(Succ(x0)), :(Char(Zero), x1))
new_span2Ys2(x0, [])
new_span2Ys13(x0, x1, x2, x3, x4)
new_span2Zs12(x0, x1, x2, Succ(x3), Succ(x4))
new_groupByZs00(Char(Succ(x0)), :(Char(Succ(x1)), x2))
new_groupByZs01(x0, x1, x2, Succ(x3), Zero)
new_span2Ys12(x0, x1, x2, Succ(x3), Succ(x4))
new_span2Ys3(:(Char(Succ(x0)), x1))
new_groupByZs01(x0, x1, x2, Succ(x3), Succ(x4))
new_span2Ys11(x0, x1, x2)
new_groupByZs02(x0, x1, x2)
We have to consider all minimal (P,Q,R)-chains.
We use the reduction pair processor [15].
The following pairs can be oriented strictly and are deleted.
new_groupBy(:(yw30, yw31)) → new_groupBy(new_groupByZs00(yw30, yw31))
The remaining pairs can at least be oriented weakly.
none
Used ordering: Polynomial interpretation [25]:
POL(:(x1, x2)) = 1 + x2
POL(Char(x1)) = 0
POL(Succ(x1)) = 0
POL(Zero) = 0
POL([]) = 0
POL(new_groupBy(x1)) = x1
POL(new_groupByZs00(x1, x2)) = x2
POL(new_groupByZs01(x1, x2, x3, x4, x5)) = 1 + x3
POL(new_groupByZs02(x1, x2, x3)) = 1 + x3
POL(new_groupByZs03(x1, x2, x3, x4, x5)) = x5
POL(new_span2Ys10(x1, x2, x3)) = 0
POL(new_span2Ys11(x1, x2, x3)) = 1 + x2
POL(new_span2Ys12(x1, x2, x3, x4, x5)) = 1 + x3
POL(new_span2Ys13(x1, x2, x3, x4, x5)) = 1 + x4
POL(new_span2Ys2(x1, x2)) = x2
POL(new_span2Ys3(x1)) = x1
POL(new_span2Zs10(x1, x2, x3)) = 1 + x3
POL(new_span2Zs11(x1, x2, x3)) = 1 + x3
POL(new_span2Zs12(x1, x2, x3, x4, x5)) = 1 + x3
POL(new_span2Zs13(x1, x2, x3, x4, x5)) = x5
POL(new_span2Zs2(x1, x2)) = x2
POL(new_span2Zs3(x1)) = x1
The following usable rules [17] were oriented:
new_span2Ys13(yw173, yw174, yw175, yw185, yw184) → :(Char(Succ(yw174)), yw185)
new_span2Zs12(yw179, yw180, yw181, Succ(yw1820), Succ(yw1830)) → new_span2Zs12(yw179, yw180, yw181, yw1820, yw1830)
new_span2Zs3(:(Char(Zero), yw3111)) → new_span2Zs10(yw3111, new_span2Ys3(yw3111), new_span2Zs3(yw3111))
new_span2Zs12(yw179, yw180, yw181, Succ(yw1820), Zero) → new_span2Zs11(yw179, yw180, yw181)
new_groupByZs03(yw90, yw91, yw92, yw100, yw99) → yw99
new_span2Zs3([]) → []
new_groupByZs00(Char(Succ(yw3000)), :(Char(Zero), yw311)) → :(Char(Zero), yw311)
new_span2Zs12(yw179, yw180, yw181, Zero, Zero) → new_span2Zs13(yw179, yw180, yw181, new_span2Ys2(yw179, yw181), new_span2Zs2(yw179, yw181))
new_span2Ys3([]) → []
new_groupByZs01(yw90, yw91, yw92, Succ(yw930), Zero) → new_groupByZs02(yw90, yw91, yw92)
new_groupByZs01(yw90, yw91, yw92, Zero, Zero) → new_groupByZs03(yw90, yw91, yw92, new_span2Ys2(yw90, yw92), new_span2Zs2(yw90, yw92))
new_groupByZs00(Char(Succ(yw3000)), :(Char(Succ(yw31000)), yw311)) → new_groupByZs01(yw3000, yw31000, yw311, yw3000, yw31000)
new_span2Zs11(yw179, yw180, yw181) → :(Char(Succ(yw180)), yw181)
new_groupByZs00(yw30, []) → []
new_span2Zs2(yw53, :(Char(Succ(yw55000)), yw551)) → new_span2Zs12(yw53, yw55000, yw551, yw53, yw55000)
new_span2Ys3(:(Char(Zero), yw3111)) → new_span2Ys11(yw3111, new_span2Ys3(yw3111), new_span2Zs3(yw3111))
new_groupByZs01(yw90, yw91, yw92, Zero, Succ(yw940)) → new_groupByZs02(yw90, yw91, yw92)
new_span2Zs10(yw3111, yw7, yw6) → yw6
new_span2Ys12(yw173, yw174, yw175, Succ(yw1760), Zero) → new_span2Ys10(yw173, yw174, yw175)
new_groupByZs00(Char(Zero), :(Char(Zero), yw311)) → new_span2Zs3(yw311)
new_span2Ys2(yw39, []) → []
new_span2Ys11(yw3111, yw5, yw4) → :(Char(Zero), yw5)
new_groupByZs01(yw90, yw91, yw92, Succ(yw930), Succ(yw940)) → new_groupByZs01(yw90, yw91, yw92, yw930, yw940)
new_span2Ys12(yw173, yw174, yw175, Succ(yw1760), Succ(yw1770)) → new_span2Ys12(yw173, yw174, yw175, yw1760, yw1770)
new_span2Zs2(yw53, :(Char(Zero), yw551)) → :(Char(Zero), yw551)
new_span2Zs3(:(Char(Succ(yw311000)), yw3111)) → :(Char(Succ(yw311000)), yw3111)
new_span2Zs13(yw179, yw180, yw181, yw187, yw186) → yw186
new_span2Ys12(yw173, yw174, yw175, Zero, Zero) → new_span2Ys13(yw173, yw174, yw175, new_span2Ys2(yw173, yw175), new_span2Zs2(yw173, yw175))
new_groupByZs00(Char(Zero), :(Char(Succ(yw31000)), yw311)) → :(Char(Succ(yw31000)), yw311)
new_span2Ys12(yw173, yw174, yw175, Zero, Succ(yw1770)) → new_span2Ys10(yw173, yw174, yw175)
new_span2Ys3(:(Char(Succ(yw311000)), yw3111)) → []
new_span2Ys2(yw39, :(Char(Zero), yw411)) → []
new_groupByZs02(yw90, yw91, yw92) → :(Char(Succ(yw91)), yw92)
new_span2Ys2(yw39, :(Char(Succ(yw41000)), yw411)) → new_span2Ys12(yw39, yw41000, yw411, yw39, yw41000)
new_span2Ys10(yw173, yw174, yw175) → []
new_span2Zs2(yw53, []) → []
new_span2Zs12(yw179, yw180, yw181, Zero, Succ(yw1830)) → new_span2Zs11(yw179, yw180, yw181)
↳ HASKELL
↳ LR
↳ HASKELL
↳ BR
↳ HASKELL
↳ COR
↳ HASKELL
↳ LetRed
↳ HASKELL
↳ Narrow
↳ AND
↳ QDP
↳ QDP
↳ QDP
↳ QDP
↳ QDP
↳ QDPOrderProof
↳ QDP
↳ PisEmptyProof
Q DP problem:
P is empty.
The TRS R consists of the following rules:
new_groupByZs00(Char(Zero), :(Char(Succ(yw31000)), yw311)) → :(Char(Succ(yw31000)), yw311)
new_groupByZs00(yw30, []) → []
new_span2Zs11(yw179, yw180, yw181) → :(Char(Succ(yw180)), yw181)
new_span2Zs13(yw179, yw180, yw181, yw187, yw186) → yw186
new_groupByZs03(yw90, yw91, yw92, yw100, yw99) → yw99
new_span2Ys3([]) → []
new_span2Zs3(:(Char(Succ(yw311000)), yw3111)) → :(Char(Succ(yw311000)), yw3111)
new_span2Zs3(:(Char(Zero), yw3111)) → new_span2Zs10(yw3111, new_span2Ys3(yw3111), new_span2Zs3(yw3111))
new_span2Ys2(yw39, :(Char(Succ(yw41000)), yw411)) → new_span2Ys12(yw39, yw41000, yw411, yw39, yw41000)
new_groupByZs02(yw90, yw91, yw92) → :(Char(Succ(yw91)), yw92)
new_span2Ys10(yw173, yw174, yw175) → []
new_groupByZs00(Char(Zero), :(Char(Zero), yw311)) → new_span2Zs3(yw311)
new_groupByZs00(Char(Succ(yw3000)), :(Char(Zero), yw311)) → :(Char(Zero), yw311)
new_groupByZs01(yw90, yw91, yw92, Zero, Zero) → new_groupByZs03(yw90, yw91, yw92, new_span2Ys2(yw90, yw92), new_span2Zs2(yw90, yw92))
new_span2Ys3(:(Char(Zero), yw3111)) → new_span2Ys11(yw3111, new_span2Ys3(yw3111), new_span2Zs3(yw3111))
new_span2Ys13(yw173, yw174, yw175, yw185, yw184) → :(Char(Succ(yw174)), yw185)
new_span2Ys11(yw3111, yw5, yw4) → :(Char(Zero), yw5)
new_span2Ys12(yw173, yw174, yw175, Zero, Succ(yw1770)) → new_span2Ys10(yw173, yw174, yw175)
new_span2Ys12(yw173, yw174, yw175, Succ(yw1760), Zero) → new_span2Ys10(yw173, yw174, yw175)
new_span2Zs2(yw53, :(Char(Succ(yw55000)), yw551)) → new_span2Zs12(yw53, yw55000, yw551, yw53, yw55000)
new_span2Zs12(yw179, yw180, yw181, Zero, Zero) → new_span2Zs13(yw179, yw180, yw181, new_span2Ys2(yw179, yw181), new_span2Zs2(yw179, yw181))
new_groupByZs01(yw90, yw91, yw92, Succ(yw930), Succ(yw940)) → new_groupByZs01(yw90, yw91, yw92, yw930, yw940)
new_span2Zs12(yw179, yw180, yw181, Succ(yw1820), Zero) → new_span2Zs11(yw179, yw180, yw181)
new_span2Zs12(yw179, yw180, yw181, Zero, Succ(yw1830)) → new_span2Zs11(yw179, yw180, yw181)
new_span2Ys2(yw39, :(Char(Zero), yw411)) → []
new_span2Ys3(:(Char(Succ(yw311000)), yw3111)) → []
new_span2Ys2(yw39, []) → []
new_span2Zs3([]) → []
new_groupByZs01(yw90, yw91, yw92, Succ(yw930), Zero) → new_groupByZs02(yw90, yw91, yw92)
new_groupByZs01(yw90, yw91, yw92, Zero, Succ(yw940)) → new_groupByZs02(yw90, yw91, yw92)
new_span2Zs12(yw179, yw180, yw181, Succ(yw1820), Succ(yw1830)) → new_span2Zs12(yw179, yw180, yw181, yw1820, yw1830)
new_span2Ys12(yw173, yw174, yw175, Succ(yw1760), Succ(yw1770)) → new_span2Ys12(yw173, yw174, yw175, yw1760, yw1770)
new_span2Ys12(yw173, yw174, yw175, Zero, Zero) → new_span2Ys13(yw173, yw174, yw175, new_span2Ys2(yw173, yw175), new_span2Zs2(yw173, yw175))
new_span2Zs2(yw53, []) → []
new_span2Zs10(yw3111, yw7, yw6) → yw6
new_groupByZs00(Char(Succ(yw3000)), :(Char(Succ(yw31000)), yw311)) → new_groupByZs01(yw3000, yw31000, yw311, yw3000, yw31000)
new_span2Zs2(yw53, :(Char(Zero), yw551)) → :(Char(Zero), yw551)
The set Q consists of the following terms:
new_span2Ys3(:(Char(Zero), x0))
new_groupByZs01(x0, x1, x2, Zero, Zero)
new_span2Zs12(x0, x1, x2, Succ(x3), Zero)
new_span2Ys2(x0, :(Char(Zero), x1))
new_groupByZs00(x0, [])
new_span2Zs12(x0, x1, x2, Zero, Succ(x3))
new_span2Zs3(:(Char(Zero), x0))
new_span2Zs11(x0, x1, x2)
new_span2Ys3([])
new_span2Zs2(x0, [])
new_groupByZs00(Char(Zero), :(Char(Succ(x0)), x1))
new_span2Zs13(x0, x1, x2, x3, x4)
new_span2Zs2(x0, :(Char(Zero), x1))
new_span2Zs3(:(Char(Succ(x0)), x1))
new_span2Ys12(x0, x1, x2, Zero, Zero)
new_span2Zs12(x0, x1, x2, Zero, Zero)
new_groupByZs00(Char(Zero), :(Char(Zero), x0))
new_span2Zs10(x0, x1, x2)
new_span2Ys12(x0, x1, x2, Zero, Succ(x3))
new_span2Zs2(x0, :(Char(Succ(x1)), x2))
new_groupByZs01(x0, x1, x2, Zero, Succ(x3))
new_span2Zs3([])
new_span2Ys2(x0, :(Char(Succ(x1)), x2))
new_groupByZs03(x0, x1, x2, x3, x4)
new_span2Ys10(x0, x1, x2)
new_span2Ys12(x0, x1, x2, Succ(x3), Zero)
new_groupByZs00(Char(Succ(x0)), :(Char(Zero), x1))
new_span2Ys2(x0, [])
new_span2Ys13(x0, x1, x2, x3, x4)
new_span2Zs12(x0, x1, x2, Succ(x3), Succ(x4))
new_groupByZs00(Char(Succ(x0)), :(Char(Succ(x1)), x2))
new_groupByZs01(x0, x1, x2, Succ(x3), Zero)
new_span2Ys12(x0, x1, x2, Succ(x3), Succ(x4))
new_span2Ys3(:(Char(Succ(x0)), x1))
new_groupByZs01(x0, x1, x2, Succ(x3), Succ(x4))
new_span2Ys11(x0, x1, x2)
new_groupByZs02(x0, x1, x2)
We have to consider all minimal (P,Q,R)-chains.
The TRS P is empty. Hence, there is no (P,Q,R) chain.